TableSyncById Function

private function TableSyncById(tables, id) result(pos)

returns the position of table in collection of tables identified by id. Arguments: tables collection of tables to search in id id of the table

Arguments

Type IntentOptional Attributes Name
type(TableCollection), intent(in) :: tables
character(len=*), intent(in) :: id

Return Value integer(kind=long)


Variables

Type Visibility Attributes Name Initial
logical, public :: foundTable
integer(kind=long), public :: i

Source Code

FUNCTION TableSyncById &
( tables, id ) &
RESULT (pos)

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringToUpper

USE LogLib, ONLY : &
! Imported Routines:
Catch

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = *),  INTENT (IN) :: id

! Type defined arguments with intent (in):
TYPE (TableCollection), INTENT (IN) :: tables

! Scalar arguments with intent(OUT):
INTEGER (KIND = long) :: pos

!Local variables:
LOGICAL :: foundTable
INTEGER (KIND = long) :: i

!------------end of declaration------------------------------------------------

foundTable = .FALSE.

DO i = 1, tables % number
  IF ( StringToUpper (tables % elem (i) % id) == StringToUpper (id) ) THEN
    foundTable = .TRUE.
    pos = i
    EXIT
  END IF
END DO

IF ( .NOT. foundTable ) THEN
  CALL Catch ('error', 'TableLib',   &
               'table not found in collection of tables: ' ,  &
		        argument = id )
END IF

END FUNCTION TableSyncById